home *** CD-ROM | disk | FTP | other *** search
- NAME ccsset
- ; File CCSSET.ASM
-
- ;CHINESE1
- ifdef MSDOS
- include mssset1.dat
- else
- include ccsset1.dat
- endif
-
- code segment public 'code'
- extrn prserr:near, comnd:near, dobaud:near, cmblnk:near, locate:near
- extrn prompt:near, coms:near, defkey:near, cwdir:near
- extrn prtscr:near, getbaud:near, isfile:near, strlen:near
- extrn strcpy:near, cnvlin:near, katoi:near, decout:near
- extrn vts:near, vtstat:near, shomodem:near, setalrm:near
-
- assume cs:code, ds:datas, es:nothing
-
- ; DO defined macro command
- ; DO macname variable variable also defines variables \%1, \%2, ...\%9
- DOCOM PROC NEAR
- mov dx,offset mcctab ; table of macro defs
- mov bx,0 ; help is table
- mov ah,cmkey ; get key word (macro name)
- call comnd ; get pointer to keyword structure
- ret
- nop
- nop
- mov comand.cmquiet,0 ; permit command echoing
- mov domacptr,bx ; address of definition string
- ; note: remtab updates domacptr because substitutions many modify the table
- mov bx,offset decbuf ; point to borrowed work buffer
- mov word ptr[bx],0 ; clear buffer
- ; mov dx,offset dohlp ; help
- mcmsg dohlp,cdohlp
- mov comand.cmblen,length rdbuf ; length of analysis buffer
- mov ah,cmtxt ; get line of text, if any
- call comnd
- ret
- nop
- nop
- mov al,ah
- mov ah,0
- mov deftemp,ax ; save byte count of command args
- cmp al,0 ; anything given?
- je docom9 ; e = no, just do the macro
- mov word ptr rdbuf+3,' 1' ; number of first variable
- docom8: mov rdbuf,0 ; clear length field, install \%x name
- mov word ptr rdbuf+1,'%\' ; start with '\%1 '
- mov word ptr rdbuf+5,0 ; clear text field
- mov tempptr,offset rdbuf+5 ; pointer to location of found word
- mov ch,0 ; make cx = 1 - 9
- mov cl,rdbuf+3 ; cx = word # of interest, for getwrd
- sub cl,'0' ; remove ascii bias
- mov si,offset decbuf ; source = work buffer (borrowed)
- call getwrd ; get CX-th word from work buf (1-9)
- cmp deftemp,0 ; length of word, was it found?
- je docom9 ; e = no, end variable definition part
- add deftemp,4 ; count '\%n ' in command line length
- call dodecom ; add keyword+def using DEF MAC below
- nop
- nop
- nop
- inc rdbuf+3 ; inc number of variable in '\%n '
- cmp rdbuf+3,'9'
- jbe docom8 ; do '1' through '9', if available
-
- ; DO the macro itself
- docom9: cmp taklev,maxtak ; room in take level?
- jl docom2 ; l = yes, continue
- ; mov dx,offset ermes4 ; else complain
- mcmsg ermes4,cermes4
- jmp reterr
- docom2: inc taklev ; increment take level
- add takadr,size takinfo
- mov bx,takadr ; point to current buffer
- mov si,domacptr ; address of macro definition string
- mov [bx].takbuf,si ; remember in Take structure
- mov cl,[si] ; length of definition
- mov ch,0
- inc si ; point to actual definition
- mov [bx].taktyp,0ffh ; flag as a macro
- mov [bx].takptr,si ; point to beginning of def
- mov [bx].takcnt,cx ; # of chars in buffer
- jmp rskp
- DOCOM ENDP
-
- ; Extract CX-th word (cx = 1-9) from buffer (DI). Enter with si = source
- ; string and tempptr pointing at destination. Returns deftemp (count) of
- ; transferred characters. Allow string in curly braces to exist as a word.
- ; Adjacent curly braced strings are separate "words":
- ; {this is word-one}{this is word-two}word-three.
- ; All registers preserved.
- getwrd proc near
- push ax
- push cx
- push dx
- push si
- push di
- push es
- push ds
- pop es ; set es to datas segment
- getwr1: push cx ; save word counter (1-9)
- mov deftemp,0 ; no bytes transferred yet
- mov di,tempptr ; where to store word/string
- mov byte ptr [di],0 ; clear destination
- mov dx,si ; start looking here in work buf
- call strlen ; cx = remaining length of work buf
- jcxz getwr6 ; z = nothing there, quit
- getwr2: lodsb
- cmp al,' ' ; skip leading whitespace
- loope getwr2
- dec si ; return to break char
- ; Parse curly brace delimited string
- ; end with si after closing brace
- mov dl,0 ; assume "opening brace" is a null
- mov dh,' ' ; assume "closing brace" is a space
- mov cx,1 ; we are at brace level 1
- cmp byte ptr [si],braceop ; starting with a real opening brace?
- jne getwr3 ; ne = no
- inc si ; skip opening brace
- mov dl,braceop ; opening brace (we count them up)
- mov dh,bracecl ; closing brace (we count them down)
- getwr3: cld ; search forward
- lodsb ; read a char
- stosb ; store in output buffer
- cmp al,0 ; at end of text?
- jne getwr3a ; ne = no
- dec si ; stay at null terminator
- dec di
- jmp short getwr6 ; we are done with this "word"
- getwr3a:inc deftemp ; count copied char
- cmp al,dl ; an opening brace?
- jne getwr4 ; ne = no
- inc cx ; yes, increment brace level
- jmp short getwr3 ; and continue scanning
-
- getwr4: cmp al,dh ; closing brace?
- jne getwr3 ; ne = no, continue scanning
- dec cx ; yes, decrement brace level
- cmp byte ptr [si],0 ; have we just read the last char?
- jne getwr5 ; no, continue scanning
- mov cx,0 ; yes, this is the closing brace
- getwr5: cmp cx,0 ; at level 0?
- jne getwr3 ; ne = no, #opening <> #closing braces
- mov byte ptr [di-1],0 ; plant terminator on closing brace
- dec deftemp ; do not count closing brace
-
- getwr6: pop cx ; recover word counter
- mov byte ptr [di],0
- jcxz getwrx ; just in case
- loop getwr1 ; do until desired word is copied
- getwrx: pop es
- pop di
- pop si
- pop dx
- pop cx
- pop ax
- ret
- getwrd endp
-
- ; DEFINE and ASSIGN macro commands
- ; Data structures comments. Macro name is stored in table mcctab as if we
- ; had used macro mkeyw, such as mkeyw 'mymac',offset my_definition.
- ; In detail: db length of name
- ; db 'name'
- ; db '$'
- ; dw offset of definition string
- ; Mcctab begins with a byte holding the number of macros in the table; one,
- ; IBM, is established at assembly time. Mcctab is 10*macmax bytes long.
- ; Pointer mccptr holds the offset of the next free byte in mcctab.
- ; Definition strings are stored in table macbuf as
- ; db length of definition string below
- ; db 'definition string'
- ; Pointer macptr holds the offset of the next free byte in macbuf. Macbuf
- ; is nominally 100*macmax bytes long.
- ; A new definition is read into buffer rdbuf+1, where byte rdbuf is reserved
- ; to hold the length of the macro's name during intermediate processing.
- ; If the definition is absent then the macro is removed from the tables.
- ; Rewritten 13 June 1987 [jrd]
- ;
- ; ASSIGN is equivalent to DEFINE, except in the definition string substitution
- ; variable names are expanded to their definitions. This becomes a copy cmd.
- ; DEFINE does not expand substitution variables.
-
- ASSIGN PROC NEAR
- mov temp,0 ; flag command as ASSIGN, vs DEFINE
- jmp dodefcom ; common code
- ASSIGN ENDP
-
- DODEF PROC NEAR
- mov temp,1 ; flag command as DEFINE, vs ASSIGN
- DODEFCOM:
- mov comand.cmper,1 ; do not react to '\%' in macro name
- mov ah,cmfile
- mov dx,offset rdbuf+1 ; buffer for macro name
- mov word ptr rdbuf,0
- ; mov bx,offset macmsg
- mcmsgb macmsg,cmacmsg
- call comnd ; get macro name
- ret
- nop
- nop
- cmp ah,0 ; null entry?
- jne dodef1 ; ne = no
- ; mov dx,offset ermes6 ; more parameters needed
- mcmsg ermes6,cermes6
- jmp reterr
-
- dodef1: mov bx,dx ; updated pointer
- mov byte ptr [bx-1],' ' ; replace null with space separator
- mov word ptr [bx],0 ; terminator, in case no command
- mov ax,temp ; get ASSIGN/DEFINE flag
- mov comand.cmper,al ; react (DEF) to '\%' in definition
- mov ah,cmtxt ; get a line of text
- ; mov dx,offset macmsg
- mcmsg macmsg,cmacmsg
- mov comand.cmblen,length rdbuf ; our buffer length
- sub comand.cmblen,al ; minus part used
- dec comand.cmblen ; space separator
- call comnd ; get macro name
- ret
- nop
- nop
- sub bx,offset rdbuf ; length of command line
- dec bx ; minus count byte
- mov deftemp,bx ; save length of command line
- ;; jmp dodecom ; common code below
- DODEF ENDP
- ; DODECOM called by DO mac above
- ; accepts rdbuf+1 et seq = <macro name><spaces><arg><spaces><arg> ...
- ; byte rdbuf computed here as length of keyword
- DODECOM PROC NEAR
- push si ; macro name in rdbuf+1 et seq
- push di ; cmd line length in deftemp
- push es
- push ds ; address data segment
- pop es
- mov cx,deftemp ; cmd line len, cx = running counter
- mov rdbuf,0 ; number of chars in keyword so far
- ; uppercase the keyword, look for end
- mov si,offset rdbuf+1 ; point at macro name text
- cld ; strings go forward
- dode2: lodsb ; get a byte, dec cx
- cmp al,'a' ; map lower case to upper
- jb dode3
- cmp al,'z'
- ja dode3
- sub al,'a'-'A'
- mov [si-1],al ; uppercase if necessary
- dode3: inc rdbuf ; increment char count of keyword
- cmp al,' ' ; is this the break character?
- loopne dode2 ; no, loop thru rest of word
- jne dode4 ; ne = did not end with break char
- dec rdbuf ; yes, don't count in length
- dode4: push di
- mov di,offset rdbuf ; point at mac name length byte
- call remtab ; remove any duplicate keyword
- pop di
- jcxz dode6 ; cx = 0 means no keyword
- ; check for free space for keyword and string
- mov al,rdbuf ; keyword text length
- add al,4 ; plus overhead bytes
- xor ah,ah
- add ax,mccptr ; add to free space pointer
- cmp ax,offset mcctab+mcclen ; enough room for name?
- jb dode5 ; b = yes
- ; mov dx,offset ermes1 ; too many macro names
- mcmsg ermes1,cermes1
- pop es
- pop di
- pop si
- jmp reterr
- dode5:
- mov di,si ; si = source address
- add di,cx ; length of string
- dec di ; omit null terminator
- std
- mov al,' ' ; scan off trailing spaces
- repe scasb
- add di,2 ; backup to terminator slot
- cld
- mov byte ptr [di],0 ; plant new terminator
- mov dx,si
- call strlen ; get new length into cx
-
- mov di,si ; scan after keyword name
- mov al,' ' ; remove leading spaces in string
- repe scasb
- je dode6 ; e = all spaces
- inc cx ; offset auto decrement of rep
- dec di ; offset auto increment of rep
-
- mov si,di ; point to start of string text
- mov dx,di ; source of definition text
- call strlen ; get length of string into cx
- mov ax,cx ; length of string
- mov deftemp,cx ; remember it here
- inc ax ; plus its count byte
- add ax,macptr ; plus free space pointer
- cmp ax,offset macbuf+maclen ; enough room for definition string?
- jb dode7 ; b = yes
- pop es
- pop di
- pop si
- ; mov dx,offset ermes2 ; no room for definition
- mcmsg ermes2,cermes2
- jmp reterr
- dode6: pop es
- pop di
- pop si
- jmp rskp
- ; install new keyword in mcctab
- dode7: cmp deftemp,0 ; deftemp = length of definition
- je dode10 ; e = no def, exit now
- mov bx,offset mcctab
- mov dx,offset rdbuf ; count byte + name string
- call addtab
- ; copy definition into buffer, changing commas to CRs
- mov di,macptr ; free space in string buffer
- mov cx,deftemp ; length of definition string
- mov byte ptr[di],cl ; store length of string
- inc di ; skip over count byte
- dode8: lodsb ; get a byte
- cmp al,',' ; comma?
- jne dode9 ; no, keep going
- mov al,cr ; else replace with cr
- dode9: stosb
- loop dode8 ; keep copying
- mov macptr,di ; update free ptr
- dode10: pop es
- pop di
- pop si
- jmp rskp
- DODECOM ENDP
-
- ; ASK <variable or macro name> <prompt string>
- ; Defines indicated variable/macro with text from user at keyboard or pipe
- ; (but not from a Take/macro). Prompt string is required. [jrd]
- ASK PROC NEAR
- mov dx,offset rdbuf+1 ; point to work buffer
- mov word ptr rdbuf,0
- ; mov bx,offset askhlp1 ; help
- mcmsgb askhlp1,caskhlp1
- mov comand.cmper,1 ; do not expand variable name
- mov ah,cmfile ; get variable name
- call comnd
- jmp r
- nop
- cmp ah,0 ; anything given?
- jne ask2 ; ne = yes
- ; mov dx,offset ermes6 ; more parameters needed
- mcmsg ermes6,cermes6
- jmp reterr
-
- ask2: xchg ah,al
- mov ah,0
- mov bx,offset rdbuf+1 ; start of name
- add bx,ax ; plus length of variable name
- mov byte ptr [bx],' ' ; put space separator after name
- inc ax ; count space
- mov temp,ax ; remember length here
- ; get ASK command prompt string
- inc bx ; put prompt string here
- mov byte ptr [bx],0 ; safety terminator
- ; mov dx,offset askhlp2
- mcmsg askhlp2,caskhlp2
- mov comand.cmblen,127 ; our buffer length
- sub comand.cmblen,al ; minus part used above
- mov ah,cmtxt ; get prompt string
- call comnd
- jmp r
- nop
- cmp ah,0 ; anything given?
- jne ask4 ; ne = yes
- ; mov dx,offset ermes6 ; more parameters needed
- mcmsg ermes6,cermes6
- jmp reterr
-
- ask4: mov ax,takadr ; we could be in a macro or Take file
- mov temp2,ax ; save Take address
- mov al,taklev
- mov ah,0
- mov temp1,ax ; and Take level
- mov dx,size takinfo ; bytes for each current Take
- mul dx ; times number of active Take/macros
- sub takadr,ax ; clear Take address as if no
- mov taklev,0 ; Take/macro were active so that
- ; user input is from kbd or pipe
- mov word ptr [bx],'$ ' ; printing terminator for prompt
- mov dx,offset rdbuf+1
- add dx,temp ; prompt for input string
- mov si,dx
- mov di,offset rdbuf+129 ; temporary destination
- push dx ; save source
- call cnvlin ; parse backslash numbers etc
- pop dx ; destination is old source location
- mov si,di ; copy back to lower part of rdbuf
- add di,cx ; go to null terminator
- mov word ptr [di],'$ ' ; dollar sign/space for DOS printing
- mov byte ptr [di+2],0
- mov di,dx
- call strcpy
- call prompt ; buf = <var name>< ><prompt string>
- mov bx,offset rdbuf+129 ; use this buffer for raw user input
- mov word ptr [bx],0 ; insert terminator
- ; mov dx,offset askhlp3 ; help for user input
- mcmsg askhlp3,caskhlp3
- mov ah,cmtxt ; read user's input string
- call comnd
- jmp ask9 ; exit now on ^C from user
- nop
- mov cl,ah ; length of entry
- mov ch,0
- jcxz ask8 ; z = empty
- mov si,offset rdbuf+129 ; source string
- mov di,offset rdbuf+1 ; start of variable name
- add di,temp ; di points to final user string
- push es ; save es
- push ds
- pop es ; set es to datas segment
- cld
- ask6: lodsb ; read original user string char
- cmp al,',' ; literal comma?
- jne ask7 ; ne = no
- mov ax,'{\' ; yes. Replace literal comma
- stosw ; with numerical equivalent \{44}
- mov ax,'44' ; to permit commas in macro def
- stosw
- add temp,4
- mov al,'}'
- ask7: stosb ; store string character
- inc temp ; length of <variable>< ><user string>
- loop ask6
- pop es
- ask8: mov ax,temp ; length of <variable>< ><user string>
- mov deftemp,ax ; put here for dodecom usage
- mov ax,temp2
- mov takadr,ax ; restore Take address
- mov ax,temp1
- mov taklev,al ; restore Take level
- jmp DODECOM ; define the macro/variable and exit
-
- ask9: mov ax,temp2 ; failure path
- mov takadr,ax ; restore Take address
- mov ax,temp1
- mov taklev,al ; restore Take level
- ret ; return command failure
- ASK ENDP
-
- ; Open a disk based Take file buffer. Define macro named "<null>T<'taklev'>",
- ; allocate 128 byte uninitiated buffer in mcctab for disk i/o. Leading null
- ; is to prevent user from employing the same name accidentally. Return offset
- ; of buffer in [takadr].takbuf and set [takadr].takptr pointing to it.
- ; Return carry clear for success, carry set for failure.
-
- TAKOPEN PROC NEAR
- push ax
- push bx
- push dx
- push di
- ; mov dx,offset ermes2 ; says no room for defintions
- mcmsg ermes2,cermes2
- mov ax,dmasiz+1 ; count byte plus length of buffer
- add ax,macptr ; plus free space pointer
- cmp ax,offset macbuf+maclen ; enough room for definition string?
- jae takopen1 ; ae = no, complain
- cmp taklev,maxtak ; room in take level?
- jl takopen2 ; l = yes, continue
- ; mov dx,offset ermes4 ; say too many Take files
- mcmsg ermes4,cermes4
- takopen1:mov ah,prstr
- int dos
- pop di
- pop dx
- pop bx
- pop ax
- stc ; set carry for failure
- ret
-
- takopen2:inc taklev ; next Take
- add takadr,size takinfo ; pointer to Take structure
- mov rdbuf,3 ; length of name, 3 bytes <null>Tn
- mov rdbuf+1,0
- mov rdbuf+2,'T' ; name of <null>Tn
- mov al,taklev ; Take level digit
- add al,'0' ; add ascii bias
- mov rdbuf+3,al ; last of the name
- mov di,offset rdbuf ; pointer for remtab
- call remtab ; remove possible old macro
- mov bx,offset mcctab ; table to use
- mov dx,offset rdbuf ; count and mac name to enter
- call addtab ; returns string pointer in macptr
- mov di,macptr
- add macptr,dmasiz+1 ; set new free byte into pointer
- mov byte ptr [di],dmasiz ; string length (128 bytes)
- mov bx,takadr ; pointer to Take structure
- mov [bx].takbuf,di ; offset of Take buffer
- inc di ; skip count byte in takbuf
- mov [bx].takptr,di ; init pointer to definition itself
- pop di
- pop dx
- pop bx
- pop ax
- clc ; carry clear for success
- ret
- TAKOPEN ENDP
-
- ; Close Take file. Enter at Take level to be closed. Removes pseudo macro
- ; name <null>Tn and its buffer, closes disk file, pops Take level.
-
- TAKCLOS PROC NEAR
- cmp taklev,0 ; anything to close?
- jle takclo2 ; le = no
- push ax
- push bx
- mov bx,takadr ; point to Take structure
- cmp [bx].taktyp,0feh ; disk file (vs macro)?
- jne takclo1 ; ne = no, no buffer to deallocate
- mov rdbuf,3 ; length of name
- mov rdbuf+1,0
- mov rdbuf+2,'T' ; name of <null>Tn
- mov al,taklev ; Take level digit
- add al,'0' ; add ascii bias
- mov rdbuf+3,al ; last of the name
- push di
- mov di,offset rdbuf ; pointer for remtab
- call remtab ; remove possible old macro
- pop di
- mov bx,[bx].takhnd ; get file handle
- mov ah,close2 ; close file
- int dos
- ; both disk and macro Takes
- takclo1:dec taklev ; pop Take level
- mov ah,taklev ; get current Take level
- mov intake,ah ; remember here for later callers
- sub takadr,size takinfo ; get previous Take's address
- pop bx
- pop ax
- takclo2:ret
- TAKCLOS ENDP
-
- ; add an entry to a keyword table
- ; enter with bx = table address, dx = ptr to new entry, macptr = string offset,
- ; mccptr = offset of free bytes in table mcctab.
- ; no check is made to see if the entry fits in the table.
- addtab proc near
- push cx
- push si
- push es
- cld
- mov ax,ds
- mov es,ax ; address data segment
- mov bp,bx ; remember where tbl starts
- mov cl,[bx] ; pick up length of table
- mov ch,0
- inc bx ; point to actual table
- jcxz addta4 ; cx = 0 if table is presently empty
-
- addta1: push cx ; preserve count
- mov si,dx ; point to entry
- lodsb ; get length of new entry
- mov cl,[bx] ; and length of table entry
- mov ah,0 ; assume they're the same size
- cmp al,cl ; are they the same?
- lahf ; remember result of comparison
- jae addta2 ; is new smaller? no, use table length
- mov cl,al ; else use length of new entry
- addta2: mov ch,0
- lea di,[bx+1] ; point to actual keyword
- repe cmpsb ; compare strings
- pop cx ; restore count
- jb addta4 ; below, insert before this one
- jne addta3 ; not below or same, keep going
- sahf ; same. get back result of length comparison
- jb addta4 ; if new len is smaller, insert here
- jne addta3 ; if not same size, keep going
- mov si,bx ; else this is where entry goes
- jmp short addta6 ; no insertion required
- addta3: mov al,[bx]
- mov ah,0
- add bx,ax ; skip this entry
- add bx,4 ; len + $ + value
- loop addta1 ; and keep looking
- addta4: mov si,bx ; this is first location to move
- mov di,bx
- inc ds:byte ptr [bp] ; remember we're adding one
- jcxz addta6 ; no more entries, forget this stuff
- mov bh,0 ; this stays 0
- addta5: mov bl,[di] ; get length
- lea di,[bx+di+4] ; end is origin + length + 4 for len, $, value
- loop addta5 ; loop thru remaining keywords
- mov cx,di
- sub cx,si ; compute # of bytes to move
- push si ; preserve loc for new entry
- mov si,di ; first to move is last
- dec si ; minus one
- mov di,dx ; new entry
- mov bl,[di] ; get length
- lea di,[bx+si+4] ; dest is source + length of new + 4
- std ; move backward
- rep movsb ; move the table down (compress it)
- cld ; put flag back
- pop si
- addta6: mov di,si ; this is where new entry goes
- mov si,dx ; this is where it comes from
- mov cl,[si] ; length
- mov ch,0
- add cx,1 ; include count byte
- add mccptr,cx ; update free space pointer: cnt+name
- add mccptr,3 ; plus '$' and pointer to string
- rep movsb ; stick it in
- mov al,'$' ; add printing terminator
- stosb
- mov ax,macptr ; and string offset
- stosw
- pop es
- pop si
- pop cx
- ret
- addtab endp
-
- ; If new keyword matches an existing one then remove existing keyword,
- ; its string definition, compress tables mcctab and macbuf, readjust string
- ; pointers for each macro name, reduce number of macro table entries by one.
- ; DO MAC pointer (domacptr) is adjusted to follow deletion.
- ; Enter with DI pointing at length byte of mac name (followed by mac name).
- ; Otherwise, exit with no changes. 13 June 1987 [jrd]
- remtab proc near
- push ax
- push bx
- push cx
- push si
- push di
- mov bx,offset mcctab+1 ; table of macro keywords
- mov temp,0 ; temp = current keyword
- cmp byte ptr mcctab,0 ; any macros defined?
- jne remta1 ; ne = yes
- jmp remtax ; else exit now
- remta1: ; match table keyword and text word
- mov si,di ; pointer to user's cnt+name
- mov cl,[si] ; length of user's macro name
- xor ch,ch
- inc si ; point to new macro name
- cmp cl,[bx] ; compare length vs table keyword
- jne remta4 ; ne = not equal lengths, try another
- push si ; lengths match, how about spelling?
- push bx
- inc bx ; point at start of keyword
- remta2: mov ah,[bx] ; keyword char
- mov al,[si] ; new text char
- cmp al,ah ; test characters
- jne remta3 ; ne = no match
- inc si ; move to next char
- inc bx
- loop remta2 ; loop through entire length
- remta3: pop bx
- pop si
- jcxz remta6 ; z: cx = 0, exit with match;
- ; else select next keyword
- remta4: inc temp ; number of keyword to test next
- mov cx,temp
- cmp cl,mcctab ; all done? Recall, temp starts at 0
- jb remta5 ; b = not yet
- jmp remtax ; exhausted search, unsuccessfully
- remta5: mov al,[bx] ; cnt (keyword length from macro)
- xor ah,ah
- add ax,4 ; skip over '$' and two byte value
- add bx,ax ; bx = start of next keyword slot
- jmp remta1 ; do another comparison
- ; new name already present as a macro
- remta6: cld ; clear macro string and macro name
- push ds
- pop es ; set es to datas segment
- mov temp,bx ; save ptr to found keyword
- mov al,[bx] ; cnt (keyword length of macro)
- xor ah,ah
- add ax,2 ; skip cnt and '$'
- add bx,ax ; point to string offset field
- add ax,2 ; count offset field bytes
- sub mccptr,ax ; readjust free space ptr for names
- push bx
- mov bx,[bx]
- mov temp1,bx ; temp1 = offset of old string
- mov al,[bx] ; length of old string
- xor ah,ah
- inc ax ; plus its count byte
- mov temp2,ax ; save here
- pop bx
- ; clear keyword table mcctab
- add bx,2 ; compute source = next keyword
- mov si,bx ; address of next keyword
- mov di,temp ; address of found keyword
- mov cx,offset mcctab+mcclen ; address of buffer end
- sub cx,si ; amount to move
- jcxz remtax ; cx = 0 means none
- rep movsb ; move down keywords (deletes current)
- ; revise other string offsets
- mov si,offset mcctab ; table of string offsets
- inc si ; skip count byte
- mov cl,mcctab ; current number of table entries
- xor ch,ch
- dec mcctab ; one less keyword
- mov dx,temp1 ; address of old string
- remta7: mov al,[si] ; cnt of first keyword
- add al,2 ; plus cnt and '$'
- xor ah,ah
- add si,ax ; look at string offset
- cmp dx,[si] ; old address vs this string
- ja remta8 ; a = address not affected
- mov ax,temp2 ; size of old string
- sub [si],ax ; adjust offset downward
- remta8: add si,2 ; point to next table entry
- loop remta7
- cmp dx,domacptr ; DO <macro> definition affected?
- ja remta8a ; a = no (occurs before removal)
- mov ax,temp2 ; get length being removed from table
- sub domacptr,ax ; revise pointer downward also
- remta8a:mov cl,taklev ; consider all Take files
- mov ch,0
- jcxz remta9 ; z = no active Take file
- ; revise Take file def pointers
- mov bx,takadr ; Take structure
- remta8b:mov ax,[bx].takbuf ; pointer to definition
- cmp dx,ax ; is this structure affected?
- ja remta8d ; a = no
- mov ax,temp2 ; length being removed from table
- sub [bx].takbuf,ax ; adjust string structure downward
- sub [bx].takptr,ax ; ditto for active read pointer
- remta8d:sub bx,size takinfo ; preceeding Take file
- loop remta8b
- ; remove old string
- remta9: mov di,temp1 ; address of old string = destination
- mov ax,temp2 ; size of old string field
- mov si,di
- add si,ax ; plus length: source = next string
- sub macptr,ax ; readjust top of buf free string ptr
- mov cx,offset macbuf+maclen ; end of buffer
- sub cx,si ; number of bytes to move
- jcxz remtax ; cx = 0 means none
- rep movsb ; move old strings (garbage collect)
- remtax: pop di
- pop si
- pop cx
- pop bx
- pop ax
- ret
- remtab endp
-
- ; Common Get keyword + Get Confirm sequence. Call with dx = keyword table,
- ; bx = help message offset. Returns result in BX. Modifies AX, BX and temp.
- ; Returns rskp if sucessful or ret if failure. Used in many places below.
- keyend proc near
- mov ah,cmkey
- call comnd
- ret
- nop
- nop
- mov temp,bx
- mov ah,cmcfm
- call comnd
- ret
- nop
- nop
- mov bx,temp
- jmp rskp
- keyend endp
-
- srvdsa proc near ; DISABLE Server commands
- mov dx,offset srvdetab
- ; mov bx,offset sdshlp
- mcmsgb sdshlp,csdshlp
- call keyend
- ret
- nop
- nop
- or denyflg,bx ; turn on bit (deny) for that item
- jmp rskp ; return successfully
- srvdsa endp
-
- srvena proc near ; ENABLE Server commands
- mov dx,offset srvdetab ; keyword table
- ; mov bx,offset sdshlp ; help on keywords
- mcmsgb sdshlp,csdshlp
- call keyend
- ret
- nop
- nop
- not bx ; invert bits
- and denyflg,bx ; turn off (enable) selected item
- jmp rskp
- srvena endp
-
-
- ; This is the SET command
- ; Called analyzers return rskp for success, else ret for failure
- SETCOM PROC NEAR ; Dispatch all SET commands from here
- mov kstatus,0 ; global status, success
- mov dx,offset settab ; Parse a keyword from the set table
- ; mov bx,offset sethlp
- mcmsgb sethlp,csethlp
- mov ah,cmkey
- call comnd
- ret
- nop
- nop
- jmp bx ; execute analyzer routine
- ; returns rskp for success, else ret
- SETCOM endp
-
- ; SET BAUD or SET SPEED
-
- BAUDST PROC NEAR
- mov dx,offset bdtab
- mov bx,0
- call keyend
- ret
- nop
- nop
- mov si,portval
- mov ax,[si].baud ; Remember original value
- mov [si].baud,bx ; Set the baud rate
- call dobaud ; Use common code
- jmp rskp
- BAUDST ENDP
-
- ; SET BELL on or off
-
- BELLST PROC NEAR
- mov dx,offset ontab
- mov bx,0
- call keyend
- ret
- nop
- nop
- mov flags.belflg,bl
- jmp rskp
- BELLST ENDP
-
- ; SET BLOCK-CHECK
-
- BLKSET PROC NEAR
- mov dx,offset blktab
- mov bx,0
- call keyend
- ret
- nop
- nop
- mov trans.chklen,bl ; Use this char as the handshake
- mov inichk,bl ; Save here too
- jmp rskp
- BLKSET ENDP
-
- ; SET COUNTER number for script IF COUNTER number <command>
- TAKECTR PROC NEAR
- mov min,0 ; get decimal char code
- mov max,65535 ; range is 0 to 65535 decimal
- mov numhlp,offset takchlp ; help message
- ;-------------- Sept.12,1990 [zqf]
- cmp isccdos,0 ; if in CCDOS ?
- je takect1 ; e = no. in MSDOS
- mov numhlp,offset ctakchlp ; help message
- takect1:
- ;--------------
- mov numerr,0 ; error message
- call num0 ; convert number, return it in ax
- jc takect2 ; c = error
- mov temp,ax ; recover numerical code
- mov ah,cmcfm
- call comnd ; Get a confirm
- ret ; Didn't get a confirm
- nop
- nop
- mov ax,temp ; recover bx
- cmp taklev,0 ; in a Take file?
- je takect4 ; e = no
- push bx
- mov bx,takadr
- mov [bx].takctr,ax ; set COUNT value
- pop bx
- takect2:jmp rskp
- takect4:
- ; mov dx,offset takcerr ; say must be in Take file
- mcmsg takcerr,ctakcerr
- jmp reterr ; display msg and jmp rskp
- TAKECTR ENDP
-
- ; SET DEBUG {OFF | ON | SESSSION | PACKETS}
-
- DEBST PROC NEAR
- mov dx,offset debtab
- ; mov bx,offset debhlp
- mcmsgb debhlp,cdebhlp
- call keyend
- ret
- nop
- nop
- or flags.debug,bl ; set the mode, except for Off
- cmp bx,0 ; OFF?
- jne deb0 ; ne = no
- mov flags.debug,0 ; Set the DEBUG flags off
- deb0: jmp rskp
- DEBST ENDP
-
- ; SET DESTINATION of incoming files
-
- DESSET PROC NEAR
- mov dx,offset destab
- mov bx,0
- call keyend
- ret
- nop
- nop
- mov flags.destflg,bl ; Set the destination flag
- cmp bl,2 ; Is dest the screen?
- jne desa ; No, then done
- mov flags.xflg,1 ; Remember it here
- jmp rskp
- desa: mov flags.xflg,0 ; Don't write to screen
- jmp rskp
- DESSET ENDP
-
- ; SET DEFAULT-DISK for sending/receiving, etc
- ; See cwdir in file mssker
-
- ; SET DELAY seconds Used only for SEND command in local mode
- SETDELY PROC NEAR
- mov min,0 ; smallest acceptable value
- mov max,63 ; largest acceptable value
- mov numhlp,offset delyhlp ; help message
- ;-------------- Sept.12,1990 [zqf]
- cmp isccdos,0 ; if in CCDOS ?
- je setdly2 ; e = no. in MSDOS
- mov numhlp,offset cdelyhlp ; help message
- setdly2:
- ;--------------
- mov numerr,0 ; complaint message
- call num0 ; parse numerical input
- jc setdly1 ; c = error
- mov trans.sdelay,al
- setdly1:jmp rskp ; success or failure
- SETDELY ENDP
-
- ; SET DISPLAY Quiet/Regular/Serial/7-Bit/8-Bit (inverse of Set Remote on/off)
- ; Accepts two keywords in one command
- disply proc near
- mov ah,cmkey
- mov dx,offset distab
- ; mov bx,offset dishlp
- mcmsgb dishlp,cdishlp
- call comnd
- ret
- nop
- nop
- mov temp1,bx ; save parsed value
- mov temp2,0ffffh ; assume no second keyword
- mov comand.cmcr,1 ; bare CR's are allowed
- mov ah,cmkey ; parse for second keyword
- mov dx,offset distab
- ; mov bx,offset dishlp
- mcmsgb dishlp,cdishlp
- call comnd
- jmp short displ1 ; no keyword
- nop
- mov temp2,bx ; get key value
- displ1: mov comand.cmcr,0 ; bare CR's are not allowed
- mov ah,cmcfm
- call comnd ; confirm
- ret ; return on failure
- nop
- nop
- mov ax,temp1 ; examine first key value
- call dispcom ; do common code
- mov ax,temp2 ; examine second key value
- call dispcom
- jmp rskp
-
- dispcom:cmp ax,0 ; check range
- jle displ3 ; le = not legal, ignore
- cmp al,7 ; 7-8 bit value?
- jge displ2 ; ge = yes
- and flags.remflg,not(dquiet+dregular+dserial)
- or flags.remflg,al ; set display mode
- ret ; check next key value
- displ2: cmp al,8 ; set 8-bit wide display?
- ja displ3 ; a = bad value
- and flags.remflg,not d8bit ; assume want 7 bit mode
- cmp al,7 ; really want 7 bit mode?
- je displ3 ; e = yes
- or flags.remflg,d8bit ; set 8 bit flag
- displ3: ret ; end of display common code
- disply endp
-
-
- ; Set Dump filename for saving screen images on disk. [jrd]
- ; Puts filename in global string dmpname
- setdmp proc near
- mov dx,offset rdbuf ; work area
- mov rdbuf,0 ; clear it
- ; mov bx,offset dmphlp ; help message
- mcmsgb dmphlp,cdmphlp
- mov ah,cmfile ; allow paths
- call comnd
- ret
- nop
- nop
- mov ah,cmcfm
- call comnd
- ret
- nop
- nop
- mov dx,offset rdbuf ; assume we will use this text
- call strlen ; filename given?
- mov si,dx ; for strcpy
- cmp cx,0 ; length of user's filename
- jg setdmp1 ; g = filename is given
- mov si,offset dmpdefnam ; no name, use default instead
- setdmp1:mov di,offset dmpname ; copy to globally available loc
- call strcpy
- jmp rskp
- setdmp endp
-
- ; SET EOF
-
- SETEOF PROC NEAR
- mov bx,0
- mov dx,offset seoftab
- call keyend
- ret
- nop
- nop
- mov flags.eofcz,bl ; set value
- jmp rskp
- SETEOF ENDP
-
- ; SET EOL char (for Sent packets)
- ; Archic, here for downward compatibility
- EOLSET PROC NEAR
- mov stflg,'S' ; set send/receive flag to Send
- jmp sreol ; use Set Send/Rec routine do the work
- EOLSET ENDP
-
- ; SET ERRORLEVEL number
- SETERL PROC NEAR
- mov numhlp,offset erlhlp ; help
- ;-------------- Sept.12,1990 [zqf]
- cmp isccdos,0 ; if in CCDOS ?
- je seterl2 ; e = no. in MSDOS
- mov numhlp,offset cerlhlp ; help message
- seterl2:
- ;--------------
- mov numerr,0 ; error message
- mov min,0 ; smallest number
- mov max,255 ; largest magnitude
- call num0 ; parse numerical input
- jc seterl1 ; c = error
- mov errlev,al ; store result
- seterl1:jmp rskp ; success or failure
- SETERL ENDP
-
- ; SET ESCAPE character.
- ; Accept literal control codes and \### numbers. [jrd] 18 Oct 1987
- ESCSET PROC NEAR
- mov ah,cmfile
- mov dx,offset rdbuf ; work space
- mov word ptr rdbuf,0 ; clear it
- ; mov bx,offset eschlp ; help
- mcmsgb eschlp,ceschlp
- call comnd
- ret
- nop
- nop
- cmp ah,0 ; anything given?
- jne escse1 ; ne = yes
- ; mov dx,offset ermes6 ; more parameters needed
- mcmsg ermes6,cermes6
- jmp reterr
- escse1: mov ah,cmcfm ; get a confirm
- call comnd
- ret
- nop
- nop
- mov si,offset rdbuf ; source of chars
- call katoi ; convert escaped numbers to binary
- cmp ax,spc ; is it a control code?
- jae escse2 ; ae = no, complain
- cmp ax,0 ; non-zero too?
- je escse2 ; e = zero
- mov trans.escchr,al ; Save new value.
- jmp rskp
- escse2:
- ; mov dx,offset escerr
- mcmsg escerr,cescerr
- jmp reterr
- ESCSET ENDP
-
- SETATT PROC NEAR ; Set attributes on | off
- mov dx,offset ontab
- mov bx,0
- call keyend
- ret
- nop
- nop
- mov flags.attflg,bl
- jmp rskp
- SETATT ENDP
-
- ; SET FILEWARNING
-
- FILWAR PROC NEAR
- mov dx,offset ontab
- mov bx,0
- call keyend
- ret
- nop
- nop
- mov flags.flwflg,bl ; Set the filewarning flag
- jmp rskp
- FILWAR ENDP
-
- ; SET FLOW-CONTROL
-
- FLOSET PROC NEAR
- mov dx,offset flotab
- xor bx,bx
- call keyend
- ret
- nop
- nop
- mov si,portval
- mov [si].flowc,bx ; Flow control value
- mov [si].floflg,bl ; Say if doing flow control
- jmp rskp
- FLOSET ENDP
-
- ; SET HANDSHAKE
- ; Add ability to accept general decimal code. [jrd]
-
- HNDSET PROC NEAR
- mov dx,offset hndtab ; table to scan
- ; mov bx,offset hnd1hlp ; help message
- mcmsgb hnd1hlp,chnd1hlp
- mov ah,cmkey
- call comnd
- ret
- nop
- nop
- cmp bl,0ffh ; want a general char code?
- jne hnd1 ; ne = no
- mov min,0 ; get decimal char code
- mov max,31 ; range is 0 to 31 decimal
- mov numhlp,offset ctlhlp ; help message
- ;-------------- Sept.12,1990 [zqf]
- cmp isccdos,0 ; if in CCDOS ?
- je hnd3 ; e = no. in MSDOS
- mov numhlp,offset cctlhlp ; help message
- hnd3:
- ;--------------
- mov numerr,0 ; error message
- call num0 ; convert number, return it in ax
- jc hnd2 ; c = error
- mov bx,ax ; recover numerical code
- hnd1:
- mov temp,bx ; handshake type
- mov ah,cmcfm
- call comnd ; Get a confirm
- ret ; Didn't get a confirm
- nop
- nop
- mov bx,temp ; recover bx
- mov si,portval
- cmp bl,0 ; Setting handshake off?
- je hnd0 ; Yes
- mov [si].hndflg,1 ; And turn on handshaking
- mov [si].hands,bl ; Use this char as the handshake
- jmp rskp
- hnd0: mov [si].hndflg,0 ; No handshaking
- hnd2: jmp rskp
- HNDSET ENDP
-
- ; SET INCOMPLETE file disposition
-
- ABFSET PROC NEAR
- mov dx,offset abftab
- mov bx,0
- call keyend
- ret
- nop
- nop
- mov flags.abfflg,bl ; Set the aborted file flag
- jmp rskp
- ABFSET ENDP
- ;
- ; Set Input commands (default-timeout, timeout-action, case, echo)
- ; By Jim Strudevant [jrs]
- INPSET PROC NEAR
- mov ah,cmkey ; key word
- mov dx,offset inptab ; from inputtable
- mov bx,0 ; no hints
- call comnd ; get the word
- ret ; they blew it
- nop
- nop
- jmp bx ; do the sub command
- ;
- ; Set Input Default-timeout in seconds
- ;
- inptmo: mov numhlp,offset intoms ; help
- ;-------------- Sept.12,1990 [zqf]
- cmp isccdos,0 ; if in CCDOS ?
- je inptmo2 ; e = no. in MSDOS
- mov numhlp,offset cintoms ; help message
- inptmo2:
- ;--------------
- mov numerr,0 ; error message
- mov min,0 ; smallest number
- mov max,-1 ; largest magnitude
- call num0 ; parse numerical input
- jc inptmo1 ; c = error
- mov script.indfto,ax ; store result
- inptmo1:jmp rskp ; success or failure
- ;
- ; Set Input Timeout action (proceed or quit)
- ;
- inpact: mov dx,offset inactb ; from this list
- mov bx,0 ; no hints
- call keyend ; get it
- ret ; bad input
- nop
- nop
- mov script.inactv,bl ; save the action
- jmp rskp ; good return
- ;
- ; Set Input Echo on or off
- ;
- inpeco: mov dx,offset ontab ; from this list
- mov bx,0 ; no hints
- call keyend ; get it
- ret ; bad input
- nop
- nop
- mov script.inecho,bl ; save the action
- jmp rskp ; good return
- ;
- ; Set Input Case observe or ignore
- ;
- inpcas: mov dx,offset incstb ; from this list
- mov bx,0 ; no hints
- call keyend ; get it
- ret ; bad input
- nop
- nop
- mov script.incasv,bl ; save the action
- jmp rskp ; good return
- INPSET ENDP
-
- ; SET KEY
- ; Jumps to new Set Key routine
- setkey proc near
- cmp stkadr,0 ; keyboard translator present?
- je setk4 ; e = no, use this routine
- mov bx,stkadr ; yes, get offset of procedure
- jmp bx ; jump to keyboard translator
- setk4:
- ; mov dx,offset ermes5
- mcmsg ermes5,cermes5
- jmp reterr ; else print error message
- setkey endp
-
- ; SET LOCAL-ECHO {ON | OFF}
-
- LCAL PROC NEAR
- mov dx,offset ontab
- mov bx,0
- call keyend
- ret
- nop
- nop
- mov si,portval
- mov [si].ecoflg,bl ; Set the local echo flag
- jmp rskp
- LCAL ENDP
-
- ; LOG {PACKETS | SESSION | TRANSACTION} filename
-
- setcpt proc near
- mov dx,offset logtab ; kinds of logging
- ; mov bx,offset loghlp ; help on kind of logging
- mcmsgb loghlp,cloghlp
- mov ah,cmkey ; parse keyword
- call comnd
- ret
- nop
- nop
- mov temp,bx ; Save the parsed value
- mov dx,offset rdbuf ; holds the complete filename
- mov rdbuf,0 ; clear buffer
- ; mov bx,offset filhlp ; ask for filename
- mcmsgb filhlp,cfilhlp
- mov ah,cmfile ; allow paths
- call comnd
- ret
- nop
- nop
- mov ah,cmcfm
- call comnd ; Get a confirm
- ret ; Didn't get a confirm
- nop
- nop
- mov bx,temp ; recover kind of logging
- mov dx,offset rdbuf ; length of filename to cx
- call strlen ; length of given filename
-
- test bl,logpkt ; packet logging?
- jz setcp2 ; z = no, try others
- mov dx,offset lpktnam ; filename
- jcxz setcp1 ; z = no filename given
- mov si,offset rdbuf ; get new name
- mov di,dx ; destination
- call strcpy ; replace old name
- setcp1: cmp ploghnd,-1 ; packet log file already open?
- je setcp6 ; e = no, open it
- jmp setcp16 ; say file is open already
-
- setcp2: test bl,logses ; session logging?
- jz setcp4 ; z = no, try others
- mov dx,offset lsesnam ; use default name
- jcxz setcp3 ; z = no filename given
- mov si,offset rdbuf ; get new name
- mov di,dx ; destination
- call strcpy ; replace old name
- setcp3: cmp sloghnd,-1 ; transaction file already open?
- je setcp6 ; e = no, open it
- jmp setcp16 ; say file is open already
-
- setcp4: test bl,logtrn ; transaction logging?
- jz setcp14 ; z = no, error
- mov dx,offset ltranam ; use default name
- jcxz setcp5 ; z = no filename given
- mov si,offset rdbuf ; get new name
- mov di,dx ; destination
- call strcpy ; replace old name
- setcp5: cmp tloghnd,-1 ; transaction file already open?
- je setcp6 ; e = no, open it
- jmp setcp16 ; say file is open already
-
- setcp6: mov ax,dx ; place for filename for isfile
- call isfile ; does file exist already?
- jc setcp7 ; c = does not exist so use create
- test byte ptr filtst.dta+21,1fh ; file attributes, ok to write?
- jnz setcp14 ; nz = no, use error exit
- mov ah,open2 ; open existing file
- mov al,1+1 ; for writing and reading
- int dos
- jc setcp14 ; if carry then error
- mov bx,ax ; file handle for seeking
- mov cx,0 ; high order displacement
- mov dx,0 ; low order part of displacement
- mov ah,lseek ; seek to EOF (to do appending)
- mov al,2 ; says to EOF
- int dos
- jmp short setcp8
-
- setcp7: test filtst.fstat,80h ; access problem?
- jnz setcp14 ; nz = yes, stop here
- mov ah,creat2 ; function is create
- mov cl,20H ; turn on archive bit
- mov ch,0
- int dos ; create the file, DOS 2.0
- jc setcp14 ; if carry bit set then error
- mov bx,ax ; file handle
-
- setcp8: cmp temp,logpkt ; packet logging?
- jne setcp9 ; ne = no
- mov ploghnd,bx ; save transaction log handle here
- jmp short setcp12
- setcp9: cmp temp,logses ; session logging?
- jne setcp10 ; ne = no
- mov sloghnd,bx ; save session log handle here
- jmp short setcp12
- setcp10:mov tloghnd,bx ; save transaction log handle here
-
- setcp12:mov ax,temp ; kind of Logging
- or flags.capflg,al ; accumulate kinds of logging
- jmp rskp ; and return
-
- setcp14:
- ; mov dx,offset errcap ; give error message
- mcmsg errcap,cerrcap
- jmp reterr ; and display it
-
- setcp16:mov ah,prstr ; file already open
- ; mov dx,offset erropn
- mcmsg erropn,cerropn
- int dos
- jmp rskp ; return success
- setcpt endp
-
- ; SET MODE LINE
-
- MODL PROC NEAR
- mov dx,offset ontab ; parse an on or off
- mov bx,0 ; no special help
- call keyend
- ret
- nop
- nop
- mov flags.modflg,bl ; set flag appropriately
- jmp rskp
- MODL ENDP
-
- ; SET PARITY
-
- SETPAR PROC NEAR
- mov dx,offset partab
- mov bx,0
- call keyend
- ret
- nop
- nop
- mov si,portval
- mov [si].parflg,bl ; Set the parity flag
- cmp bl,parnon ; Resetting parity to none?
- je setp0 ; e = yes, reset 8 bit quote character
- mov trans.ebquot,dqbin ; we want quoting, active
- mov dtrans.ebquot,dqbin ; we want quoting, our default
- jmp short setp1
- setp0: mov trans.ebquot,'Y' ; say will quote upon request
- mov dtrans.ebquot,'Y' ; and our default
- setp1: jmp rskp
- SETPAR ENDP
-
- ; SET PROMPT Allow user to change the "Kermit-MS>" prompt
- ; {string} and \number notation permitted to represent special chars. [jrd]
-
- PROMSET PROC NEAR
- mov ah,cmtxt
- mov bx,offset rdbuf ; Read in the prompt
- mov word ptr [bx],0 ; clear buffer
- ; mov dx,offset prmmsg
- mcmsg prmmsg,cprmmsg
- call comnd
- ret
- nop
- nop
- cmp rdbuf,0 ; Just a bare CR?
- jne prom0 ; ne = no
- mov ax,offset kerm ; yes, restore default prompt
- jmp prom1
- prom0: push si ; parse \### constants into
- push di ; 1 byte binary numbers inline
- mov si,offset rdbuf ; source = new prompt string
- mov byte ptr [si-1+length rdbuf],0 ; plant null terminator
- mov di,offset prm ; destination
- call cnvlin ; convert \### in string to binary
- pop di
- pop si
- mov bx,cx ; get byte count
- add bx,offset prm ; point to null terminator
- mov byte ptr [bx],'$' ; End of string
- mov ax,offset prm
- prom1: mov prmptr,ax ; Remember it
- jmp rskp
- PROMSET ENDP
-
- ; SET SERVER TIMEOUT
-
- SETSRV PROC NEAR
- mov dx,offset srvtab ; set server table
- mov bx,0 ; use table for help
- mov ah,cmkey ; get keyword
- call comnd
- ret
- nop
- nop
- mov min,0 ; smallest acceptable value
- mov max,255 ; largest acceptable value, one byte
- mov numhlp,offset srvthlp ; help message
- ;-------------- Sept.12,1990 [zqf]
- cmp isccdos,0 ; if in CCDOS ?
- je setsrv2 ; e = no. in MSDOS
- mov numhlp,offset csrvthlp ; help message
- setsrv2:
- ;--------------
- mov numerr,0 ; complaint message
- call num0 ; parse numerical input
- jc setsrv1 ; c = error
- mov srvtmo,al ; store timeout value
- setsrv1:jmp rskp
- SETSRV ENDP
-
- ; SET RETRY value. Changes the packet retry limit. [jrd]
-
- RETRYSET PROC NEAR
- mov min,1 ; smallest acceptable value
- mov max,63 ; largest acceptable value
- mov numhlp,offset retryhlp ; help message
- ;-------------- Sept.12,1990 [zqf]
- cmp isccdos,0 ; if in CCDOS ?
- je retrys2 ; e = no. in MSDOS
- mov numhlp,offset cretryhlp ; help message
- retrys2:
- ;--------------
- mov numerr,0 ; complaint message
- call num0 ; parse numerical input
- jc retrys1 ; c = error
- mov maxtry,al
- shl al,1 ; quick multiply by two or three
- mov imxtry,al ; keep that much
- add al,maxtry ; try three times
- js retrys1 ; s = sign bit set, too much
- mov imxtry,al ; I packets get 3 times as many tries
- retrys1:jmp rskp
- RETRYSET ENDP
-
- ; SET TAKE-ECHO on or off
-
- TAKSET PROC NEAR
- mov dx,offset ontab
- mov bx,0
- call keyend
- ret
- nop
- nop
- mov flags.takflg,bl
- jmp rskp
- TAKSET ENDP
-
- ; SET TIMER on or off during file transfer
-
- TIMSET PROC NEAR
- mov dx,offset ontab
- mov bx,0
- call keyend
- ret
- nop
- nop
- mov flags.timflg,bl
- jmp rskp
- TIMSET ENDP
-
- ; SET SEND parameters
-
- SENDSET PROC NEAR
- mov stflg,'S' ; Setting SEND parameter
- sndst0: mov dx,offset stsrtb ; Parse a keyword
- mov bx,0 ; no specific help
- mov ah,cmkey
- call comnd
- ret ; bad user text
- nop
- nop
- jmp bx ; do the action routine
- SENDSET ENDP
-
- ; SET RECEIVE parameters
-
- recset: mov stflg,'R' ; Setting RECEIVE paramter
- jmp sndst0
-
- remset proc near ; Set REMOTE ON/OFF
- mov dx,offset ontab
- ; mov bx,offset remhlp
- mcmsgb remhlp,cremhlp
- call keyend
- ret
- nop
- nop
- and flags.remflg,not (dquiet+dserial+dregular) ; no display bits
- or bl,bl ; want off state? (same as regular)
- jz remset1 ; z = yes
- or flags.remflg,dquiet ; else on = quiet display
- jmp short remset2
- remset1:or flags.remflg,dregular ; off = regular display
- remset2:jmp rskp
- remset endp
-
-
- ; SET Send and Receive EOL char
-
- sreol PROC NEAR
- mov min,0 ; lowest acceptable value
- mov max,1FH ; largest acceptable value
- mov numhlp,offset ctlhlp ; Reuse help message
- ;-------------- Sept.12,1990 [zqf]
- cmp isccdos,0 ; if in CCDOS ?
- je sreol4 ; e = no. in MSDOS
- mov numhlp,offset cctlhlp ; help message
- sreol4:
- ;--------------
- mov numerr,0 ; error message address
- call num0 ; get numerical input
- jc sreol3 ; c = error
- cmp stflg,'S' ; Setting SEND paramter?
- je sreol1
- mov trans.reol,al
- jmp short sreol2
- sreol1: mov dtrans.seol,al
- sreol2: mov ah,dtrans.seol
- mov trans.seol,ah
- sreol3: jmp rskp
- sreol ENDP
-
-
- ; SET SEND and RECEIVE start-of-header
-
- srsoh: mov min,0
- mov max,1FH
- mov numhlp,offset ctlhlp ; Reuse help message
- ;-------------- Sept.12,1990 [zqf]
- cmp isccdos,0 ; if in CCDOS ?
- je srsoh3 ; e = no. in MSDOS
- mov numhlp,offset cctlhlp ; help message
- srsoh3:
- ;--------------
- mov numerr,0 ; error message
- call num0 ; Common routine for parsing numerical input
- jc srsoh2 ; c = error
- cmp stflg,'S' ; Setting SEND paramter?
- je srsoh1
- mov trans.rsoh,al ; set Receive soh
- jmp short srsoh2
- srsoh1: mov trans.ssoh,al ; set Send soh
- srsoh2: jmp rskp ; success or failure
-
- ; SET SEND and RECEIVE TIMEOUT
-
- srtim: mov min,0
- mov max,94
- mov numhlp,offset timhlp ; Reuse help message
- ;-------------- Sept.12,1990 [zqf]
- cmp isccdos,0 ; if in CCDOS ?
- je srtim4 ; e = no. in MSDOS
- mov numhlp,offset ctimhlp ; help message
- srtim4:
- ;--------------
- mov numerr,0 ; error message
- call num0 ; Common routine for parsing numerical input
- jc srtim3 ; c = error
- cmp stflg,'S' ; Setting SEND paramter?
- je srtim1
- mov trans.rtime,al
- jmp short srtim2
- srtim1: mov dtrans.stime,al
- srtim2: mov ah,dtrans.stime
- mov trans.stime,ah
- srtim3: jmp rskp
-
- ; SET SEND and RECEIVE PACKET LENGTH
-
- srpack: mov min,20
- mov max,maxpack
- mov numhlp,offset pakhlp ; help
- ;-------------- Sept.12,1990 [zqf]
- cmp isccdos,0 ; if in CCDOS ?
- je srpak5 ; e = no. in MSDOS
- mov numhlp,offset cpakhlp ; help message
- srpak5:
- ;--------------
- mov numerr,offset pakerr ; error message
- ;-------------- Sept.12,1990 [zqf]
- cmp isccdos,0 ; if in CCDOS ?
- je srpak6 ; e = no. in MSDOS
- mov numerr,offset cpakerr ; help message
- srpak6:
- ;--------------
- call num0
- jc srpak2 ; c = error
- cmp stflg,'S' ; setting send value?
- jne srpakr ; ne = receive
- mov trans.slongp,ax ; set send value
- mov trans.slong,ax ; and remember what we Set
- cmp ax,94 ; within normal packet range?
- ja srpak2 ; a = no
- mov trans.spsiz,al ; yes. update regular pkt size too
- srpak2: jmp rskp ; success or failure
- srpakr: mov trans.rlongp,ax ; set receive value
- cmp ax,94 ; within normal packet range?
- ja srpak4 ; a = no
- mov trans.rpsiz,al ; yes. update regular pkt size too
- srpak4: jmp rskp
-
-
- ; SET SEND and RECEIVE number of padding characters
-
- srnpd: mov min,0
- mov max,99
- mov numhlp,offset padhlp ; help message
- ;-------------- Sept.12,1990 [zqf]
- cmp isccdos,0 ; if in CCDOS ?
- je srnpd4 ; e = no. in MSDOS
- mov numhlp,offset cpadhlp ; help message
- srnpd4:
- ;--------------
- mov numerr,0 ; error message
- call num0 ; Parse numerical input
- jc srnpd3 ; c = error
- cmp stflg,'S' ; Setting SEND paramter?
- je srnpd1 ; e = yes
- mov trans.rpad,al ; set Receive padding
- jmp short srnpd2
- srnpd1: mov dtrans.spad,al ; set default Send padding
- srnpd2: mov al,dtrans.spad
- mov trans.spad,al ; update active array for I and S pkts
- srnpd3: jmp rskp ; success or failure
-
- ; SET SEND and RECEIVE padding character
-
- srpad: mov min,0
- mov max,127
- mov numhlp,offset padhlp
- ;-------------- Sept.12,1990 [zqf]
- cmp isccdos,0 ; if in CCDOS ?
- je srpad5 ; e = no. in MSDOS
- mov numhlp,offset cpadhlp ; help message
- srpad5:
- ;--------------
- mov numerr,offset padhlp
- ;-------------- Sept.12,1990 [zqf]
- cmp isccdos,0 ; if in CCDOS ?
- je srpad6 ; e = no. in MSDOS
- mov numerr,offset cpadhlp ; help message
- srpad6:
- ;--------------
- call num0 ; Parse numerical input
- jc srpad4 ; c = error
- cmp ah,127 ; This is allowed
- je srpad1
- cmp ah,32
- jb srpad1 ; Between 0 and 31 is OK too
- mov ah,prstr
- ; mov dx,offset padhlp
- mcmsg padhlp,cpadhlp
- int dos
- srpad1: cmp stflg,'S' ; Send?
- je srpad2 ; e = yes, else Receive
- mov trans.rpadch,al ; store receive pad char
- jmp short srpad3
- srpad2: mov dtrans.spadch,al ; store Send pad char
- srpad3: mov ah,dtrans.spadch
- mov trans.spadch,ah ; update active array for I and S pkts
- srpad4: jmp rskp
-
- ; SET SEND and RECEIVE control character prefix
-
- srquo: mov min,33
- mov max,126
- mov numhlp,offset quohlp ; help message
- ;-------------- Sept.12,1990 [zqf]
- cmp isccdos,0 ; if in CCDOS ?
- je srquo4 ; e = no. in MSDOS
- mov numhlp,offset cquohlp ; help message
- srquo4:
- ;--------------
- mov numerr,0 ; error message
- call num0 ; Parse numerical input
- jc srquo3 ; c = error
- cmp stflg,'S' ; Setting outgoing quote char?
- je srquo1
- mov trans.rquote,al ; set Receive quote char
- jmp short srquo2
- srquo1: mov dtrans.squote,al ; set Send quote char
- srquo2: mov ah,dtrans.spadch
- mov trans.spadch,ah ; update active array for I and S pkts
- srquo3: jmp rskp
-
- ; SET SEND Pause number of milliseconds
-
- srpaus: mov min,0
- mov max,127
- mov numhlp,offset pauhlp ; help
- ;-------------- Sept.12,1990 [zqf]
- cmp isccdos,0 ; if in CCDOS ?
- je srpau4 ; e = no. in MSDOS
- mov numhlp,offset cpauhlp ; help message
- srpau4:
- ;--------------
- mov numerr,0
- call num0 ; Parse numerical input
- pushf ; save carry for error state
- cmp stflg,'S' ; Setting SEND paramter?
- je srpau0
- popf
- ; mov dx,offset ermes5 ; "Not implemented" msg
- mcmsg ermes5,cermes5
- jmp reterr ; print error message
- srpau0: popf
- jc srpau1 ; c = error
- mov spause,al ; store value
- srpau1: jmp rskp
-
- ; SET TRANSLATION INPUT Connect mode translate incoming characters
- ; SET TRANS IN {Original-byte New-byte | ON | OFF}
-
- SETRX PROC NEAR ; translate incoming serial port char
- mov ah,cmkey
- mov dx,offset trnstab ; direction table (just one entry)
- mov bx,0 ; no help
- call comnd
- ret
- nop
- nop
- mov dx,offset rdbuf ; our work space
- mov word ptr rdbuf,0 ; insert terminator
- ; mov bx,offset srxhlp1 ; first help message
- mcmsgb srxhlp1,csrxhlp1
- mov ah,cmfile ; parse a word
- call comnd ; get incoming byte pattern
- ret ; error if none
- nop
- nop
- or ah,ah ; any text given?
- jz setr6 ; nz = no
- mov temp,ax ; save byte count here
- mov ax,word ptr rdbuf ; get first two characters
- or ax,2020h ; convert upper to lower case
- cmp ax,'fo' ; first part of word OFF?
- je setr6 ; e = yes, go analyze
- cmp ax,'no' ; word ON?
- je setr6 ; e = yes, go do it
- mov si,offset rdbuf ; convert text to number
- call katoi ; number converter procedure, to ax
- jnc setr1 ; nc = success
- cmp byte ptr temp+1,1 ; just one character given?
- jne setr6 ; ne = no, so bad code
- setr1: mov min,ax ; save byte code here
- mov dx,offset rdbuf ; our work space
- mov word ptr rdbuf,0 ; insert terminator
- ; mov bx,offset srxhlp1 ; first help message
- mcmsgb srxhlp1,csrxhlp1
- mov ah,cmfile ; parse a word
- call comnd ; get incoming byte pattern
- ret
- nop
- nop
- or ah,ah ; any text given?
- jz setr6 ; z = no
- mov temp,ax ; save byte count here
- mov si,offset rdbuf ; convert text to number
- call katoi ; number converter procedure
- jnc setr3 ; nc = success
- cmp byte ptr temp+1,1 ; just one character given?
- jne setr6 ; ne = no, so bad code or ON/OFF
- setr3: mov max,ax ; save byte code here
- mov ah,cmcfm ; get a confirm
- call comnd
- ret ; no confirm
- nop
- nop
- mov bx,min ; bl = incoming byte code
- xor bh,bh
- mov ax,max ; al = local (translated) byte code
- mov rxtable [bx],al ; store in rx translate table
- jmp rskp
-
- setr6: mov ah,cmcfm ; get a confirm
- call comnd
- ret
- nop
- nop
- ; mov dx,offset badrx ; assume bad construction
- mcmsg badrx,cbadrx
- or word ptr rdbuf,2020h ; convert to lower case
- or rdbuf+2,20h ; first three chars
- cmp word ptr rdbuf,'fo' ; key word OFF?
- jne setr8 ; ne = no
- cmp rdbuf+2,'f' ; last letter of OFF?
- jne setr8
- mov rxtable+256,0 ; OFF is status byte = zero
- ; mov dx,offset rxoffmsg ; say translation is turned off
- mcmsg rxoffmsg,crxoffmsg
- jmp setr9
- setr8: cmp word ptr rdbuf,'no' ; keyword ON?
- jne setr9a ; ne = no, error
- mov rxtable+256,1 ; ON is status byte non-zero
- ; mov dx,offset rxonmsg ; say translation is turned on
- mcmsg rxonmsg,crxonmsg
- setr9: cmp intake,0 ; executing from a Take file?
- je setr9a ; e = no
- cmp flags.takflg,0 ; echo contents of Take file?
- je setr10 ; e = no
- setr9a: mov ah,prstr ; bad number message
- int dos
- setr10: jmp rskp
- SETRX ENDP
-
- ; SHOW TRANSLATE-RECEIVE
- ; Display characters being changed for Connect mode serial receive translator
-
- SHORX PROC NEAR ; show translate table of incoming
- ; chars, only those changed
- mov ah,cmcfm ; get a confirm
- call comnd
- ret ; no confirm
- nop
- nop
- mov ah,prstr
- ; mov dx,offset rxoffmsg ; assume translation is off
- mcmsg rxoffmsg,crxoffmsg
- cmp rxtable+256,0 ; is translation off?
- je shorx0 ; e = yes
- ; mov dx,offset rxonmsg ; say translation is on
- mcmsg rxonmsg,crxonmsg
- shorx0: int dos
- ; mov dx,offset shormsg ; give title line
- mcmsg shormsg,cshormsg
- int dos
- xor cx,cx ; formatted line counter
- xor bx,bx ; entry subscript
- shorx1: cmp rxtable[bx],bl ; entry same as normal?
- je shorx2 ; e = yes, skip it
- call shoprt ; print the entry
- shorx2: inc bx ; next entry
- cmp bx,255 ; done all entries yet?
- jbe shorx1 ; be = not yet
- mov ah,prstr
- mov dx,offset crlf ; end with cr/lf
- int dos
- jmp rskp
-
- shoprt: cmp cx,4 ; done five entries for this line?
- jb shopr1 ; b = no
- mov ah,prstr
- mov dx,offset crlf ; break line now
- int dos
- xor cx,cx
- shopr1: mov ah,prstr
- mov dx,offset shopm1 ; start of display
- int dos
- xor ah,ah
- mov al,bl ; original byte code
- call decout ; display its value
- mov ah,prstr
- mov dx,offset shopm2 ; intermediate part of display
- int dos
- xor ah,ah
- mov al,rxtable[bx] ; new byte code
- call decout ; display its value
- mov ah,prstr
- mov dx,offset shopm3 ; last part of display
- int dos
- inc cx ; count item displayed
- ret
- SHORX ENDP
-
- ; SHOW MACRO [macro name]
-
- SHOMAC PROC NEAR
- mov ah,cmfile
- mov dx,offset rdbuf
- ; mov bx,offset shmmsg
- mcmsgb shmmsg,cshmmsg
- mov comand.cmper,1 ; don't react to \%x variables
- call comnd
- ret
- nop
- nop
- mov al,ah
- mov ah,0
- mov shmcnt,ax ; save length of user spec
- mov ah,cmcfm
- call comnd
- ret
- nop
- nop
- mov si,offset mcctab ; table of macro names
- cld
- lodsb
- mov cl,al ; number of macro entries
- mov ch,0
- jcxz shom6 ; z = none
- mov temp,0 ; count of macros displayed
- shom2: push cx ; save loop counter
- lodsb ; length of macro name
- mov ah,0
- mov cx,shmcnt ; length of user's string
- jcxz shom4 ; show all names
- cmp al,cl ; mac name shorter that user spec?
- jb shom5 ; b = yes, no match
- push ax
- push si ; save these around match test
- mov di,offset rdbuf ; user's string
- shom3: mov ah,[di]
- inc di
- lodsb ; al = mac name char, ah = user char
- and ax,not 2020h ; clear bits (uppercase chars)
- cmp ah,al ; same?
- loope shom3 ; while equal, do more
- pop si ; restore regs
- pop ax
- jne shom5 ; ne = no match
- shom4: call shom9 ; show this name
- shom5: add si,ax ; no match, skip name
- add si,3 ; and '$', and string pointer
- pop cx ; recover loop counter
- loop shom2 ; one less macro to examine
-
- cmp temp,0 ; did we show any macros?
- jne shom7 ; ne = yes
- shom6: mov ah,prstr
- ; mov dx,offset shom9m3 ; no entries found
- mcmsg shom9m3,cshom9m3
- int dos
- shom7: mov ah,prstr ; Summary line
- ; mov dx,offset shom9m1 ; free space: name entries
- mcmsg shom9m1,cshom9m1
- int dos
- mov ax,offset mcctab+mcclen
- sub ax,mccptr ; compute # of free name bytes
- call decout
- mov ah,prstr
- ; mov dx,offset shom9m2 ; body characters
- mcmsg shom9m2,cshom9m2
- int dos
- mov ax,offset macbuf+maclen
- sub ax,macptr
- call decout
- mov ah,prstr
- mov dx,offset crlf
- int dos
- jmp rskp ; return successfully to caller
-
- ; worker, show mac name and def
- shom9: push ax ; call with si pointing at macro
- push si ; name, byte ptr [si-1] = length
- cmp byte ptr[si],0 ; name starts with null char?
- je shom9e ; yes, TAKE file, ignore
- mov ah,prstr
- mov dx,offset crlfsp ; go to new line
- int dos
- inc temp ; count displayed macros
- mov dx,si ; Print macro name
- int dos
- mov dx,offset eqs ; display equals sign
- int dos
- mov al,[si-1] ; length of macro name
- mov ah,0
- add si,ax ; skip over name
- add si,1 ; skip '$' field
- mov si,[si] ; si = offset of count + string
- mov cl,byte ptr [si] ; length of string
- mov ch,0
- inc si ; si = offset of string text proper
- shom9a: lodsb ; get a byte into al
- cmp al,' ' ; control char?
- jae shom9c ; ae = no
- cmp al,cr ; carriage return?
- jne shom9b ; ne = no
- mov ah,prstr
- mov dx,offset shom9m4 ; show <cr>
- int dos
- cmp cx,1 ; more to show?
- je shom9d ; e = no
- mov dx,offset crlfsp ; show cr,lf,space,space
- int dos
- cmp byte ptr[si],lf ; cr followed by linefeed?
- jne short shom9d
- inc si ; skip the leading lf
- dec cx
- jmp short shom9d
- shom9b: push ax
- mov ah,conout
- mov dl,5eh ; caret
- int dos
- pop ax
- add al,'A'-1 ; add offset to make printable letter
- shom9c: mov ah,conout
- mov dl,al ; display it
- int dos
- shom9d: loop shom9a ; do whole string
- shom9e: pop si
- pop ax
- ret
- SHOMAC ENDP
-
- SHCOM PROC NEAR ; Show Modem
- mov ah,cmcfm
- call comnd ; Get a confirm
- ret ; Didn't get a confirm
- nop
- nop
- mov dx,offset crlf
- mov ah,prstr
- int dos ; print a crlf
- ; mov bx,offset stcom ; table of items to be shown
- mcmsgb stcom,cstcom
- call statc ; finish in common code
- nop
- nop
- nop
- call shomodem
- nop
- nop
- nop
- jmp rskp
- SHCOM ENDP
- SHFILE PROC NEAR ; Show File
- mov ah,cmcfm
- call comnd ; Get a confirm
- ret ; Didn't get a confirm
- nop
- nop
- mov dx,offset crlf
- mov ah,prstr
- int dos ; print a crlf
- ; mov bx,offset stfile ; table of items to be shown
- mcmsgb stfile,cstfile
- jmp statc ; finish in common code
- SHFILE ENDP
-
- SHLOG PROC NEAR ; Show Log
- mov ah,cmcfm
- call comnd ; Get a confirm
- ret
- nop
- nop
- mov dx,offset crlf
- mov ah,prstr
- int dos ; print a crlf
- ; mov bx,offset stlog ; table of items to be shown
- mcmsgb stlog,cstlog
- jmp statc ; finish in common code
- SHLOG ENDP
- SHPRO PROC NEAR ; Show Protocol
- mov ah,cmcfm
- call comnd ; Get a confirm
- ret
- nop
- nop
- mov dx,offset crlf
- mov ah,prstr
- int dos ; print a crlf
- ; mov bx,offset stpro ; table of items to be shown
- mcmsgb stpro,cstpro
- jmp statc ; finish in common code
- SHPRO ENDP
- SHSCPT PROC NEAR ; Show Script
- mov ah,cmcfm
- call comnd ; Get a confirm
- ret
- nop
- nop
- mov dx,offset crlf
- mov ah,prstr
- int dos ; print a crlf
- ; mov bx,offset stscpt ; table of items to be shown
- mcmsgb stscpt,cstscpt
- jmp statc ; finish in common code
- SHSCPT ENDP
- SHSERV PROC NEAR ; Show Server
- mov ah,cmcfm
- call comnd ; Get a confirm
- ret
- nop
- nop
- mov dx,offset crlf
- mov ah,prstr
- int dos ; print a crlf
- ; mov bx,offset stserv2 ; do heartbeak item
- mcmsgb stserv2,cstserv2
- call statc
- nop
- nop
- nop
- mov dx,offset crlf
- mov ah,prstr
- int dos
- ; mov bx,offset stserv ; table of items to be shown
- mcmsgb stserv,cstserv
- jmp statc ; finish in common code
- SHSERV ENDP
-
- SHTERM PROC NEAR ; Show Terminal
- mov ah,cmcfm
- call comnd ; Get a confirm
- ret
- nop
- nop
- mov dx,offset crlf
- mov ah,prstr
- int dos ; print a crlf
- ; mov bx,offset stterm ; table of items to be shown
- mcmsgb stterm,cstterm
- jmp statc ; use common code
- SHTERM ENDP
-
- ; STATUS command. Revised by [jrd]
-
- STATUS PROC NEAR
- mov ah,cmcfm
- call comnd ; Get a confirm
- ret
- nop
- nop
- mov dx,offset crlf
- mov ah,prstr
- int dos ; print a crlf
- STAT0: call cmblnk ; clear the screen
- call locate ; home the cursor
- ; mov bx,offset sttab ; table to control printing
- mcmsgb sttab,csttab
-
- STATC: push es ; STAT0 is an external ref (in mster)
- push di
- mov cx,ds
- mov es,cx
- cld
- xor cx,cx ; column counter
- stat1: cmp word ptr [bx],0 ; end of table?
- je statx ; e = yes
- cld ; string direction is forward
- mov di,offset rdbuf ; point to destination buffer
- mov byte ptr[di],spc ; start with two spaces
- inc di
- mov byte ptr[di],spc
- inc di
- push cx ; save column number
- push bx
- call [bx].sttyp ; call appropriate routine
- pop bx
- pop cx
- sub di,offset rdbuf ; number of bytes used
- add cx,di ; new line col count
- push cx ; save col number around print
- mov cx,di ; how much to print now
- mov di,offset rdbuf ; source text
- cmp cx,2 ; nothing besides our two spaces?
- jbe stat5 ; e = yes, forget it
- call prtscr ; print counted string
- stat5: pop cx
- add bx,size stent ; look at next entry
- cmp word ptr [bx],0 ; at end of table?
- je statx ; e = yes
- cmp cx,38 ; place for second display?
- jbe stat2 ; be = only half full
- mov dx,offset crlf ; over half full. send cr/lf
- mov ah,prstr
- int dos
- xor cx,cx ; say line is empty now
- jmp stat1
- stat2: mov ax,cx
- mov cx,38 ; where we want to be next time
- sub cx,ax ; compute number of filler spaces
- or cx,cx
- jle stat4 ; nothing to do
- mov ah,conout
- mov dl,' '
- stat3: int dos ; fill with spaces
- loop stat3 ; do cx times
- stat4: mov cx,38 ; current column number
- jmp stat1 ; and do it
- statx: pop di
- pop es
- jmp rskp
- STATUS ENDP
-
- ; handler routines for status
- ; all are called with di/ destination buffer, bx/ stat ptr. They can change
- ; any register except es:, must update di to the end of the buffer.
-
- ; copy the message into the buffer
- stmsg proc near
- push ds
- pop es ; ensure es points to datas segment
- mov si,[bx].msg ; get message address
- stms1: lodsb ; get a byte
- stosb ; drop it off
- cmp al,'$' ; end of message?
- jne stms1 ; no, keep going
- dec di ; else back up ptr
- ret
- stmsg endp
-
- ; get address of test value in stent. Returns address in si
- stval proc near
- mov si,[bx].basval ; get base value
- cmp si,0 ; any there?
- je stva1 ; no, keep going
- mov si,[si] ; yes, use as base address
- stva1: add si,[bx].tstcel ; add offset of test cell
- ret ; and return it
- stval endp
-
- ; print a single character
- onechr proc near
- call stmsg ; copy message part first
- call stval ; pick up test value address
- mov al,[si] ; this is char to print
- cmp al,' ' ; printable?
- jae onech1 ; yes, keep going
- add al,64 ; make printable
- mov byte ptr [di],5eh ; caret
- inc di ; note ctrl char
- onech1: stosb ; drop char off
- ret
- onechr endp
-
- ; numeric field
- stnum proc near ; for 8 bit numbers
- call stmsg ; copy message
- call stval ; pick up value address
- mov al,[si] ; get value
- mov ah,0 ; high order is 0
- call outnum ; put number into buffer
- ret
- stnum endp
-
- stlnum proc near ; for 16 bit numbers [jrd]
- call stmsg ; copy message
- call stval ; pick up value address
- mov ax,[si] ; get value
- call outnum ; put number into buffer
- ret
- stlnum endp
-
- ; Common routine for parsing numerical input
- ; Enter with numhlp = offset of help message, numerr = offset of optional
- ; error message, min, max = allowable range of values.
- ; Returns value in ax, or does parse error return.
- ; Changes ax,bx,dx,si. [jrd] 18 Oct 1987
- num0: mov dx,offset rdbuf+1 ; were to put text
- mov word ptr rdbuf,0 ; clear the buffer
- mov bx,numhlp ; help text
- mov ah,cmfile ; get a word
- call comnd
- ret
- nop
- nop
- mov ah,cmcfm
- call comnd ; Get a confirm
- ret
- nop
- nop
- mov si,offset rdbuf+1
- cmp rdbuf+1,'\' ; already quoted?
- je num0a ; e = yes
- mov rdbuf,'\' ; add a numerical quote
- dec si ; point to our escape char
- num0a: call katoi ; convert number in rdbuf
- jc num0er ; c = no number, error
- cmp ax,max ; largest permitted value
- ja num0er ; a = error
- cmp ax,min ; smallest permitted value
- jb num0er ; b = error
- clc
- ret ; return value in ax
-
- num0er: mov ah,prstr
- mov dx,numerr ; comand-specific error message, if any
- cmp dx,0 ; was any given?
- je num0e1 ; e = no, use generic msg
- int dos ; show given error message
- jmp short num0e2
- num0e1:
- ; mov dx,offset nummsg1 ; get address of numeric error message
- mcmsg nummsg1,cnummsg1
- int dos
- mov ax,min ; smallest permitted number
- call decout ; display decimal number in ax
- mov ah,prstr
- ; mov dx,offset nummsg2 ; "and"
- mcmsg nummsg2,cnummsg2
- int dos
- mov ax,max ; largest permitted number
- call decout
- num0e2: stc
- ret
- num0e3: mov ah,prstr
- ; mov dx,offset ermes7 ; say command not executed
- mcmsg ermes7,cermes7
- int dos
- stc
- ret
-
- ; translate the number in ax
- outnum proc near
- mov dx,0
- mov bx,10
- div bx ; divide to get digit
- push dx ; save remainder digit
- or ax,ax ; test quotient
- jz outnu1 ; zero, no more of number
- call outnum ; else call for rest of number
- outnu1: pop ax ; get digit back
- add al,'0' ; make printable
- stosb ; drop it off
- ret
- outnum endp
-
- ; on/off field
- onoff proc near
- call stmsg ; copy message
- call stval ; get value cell
- mov al,[si]
- mov si,offset onmsg
- mov cx,2 ; assume 2-byte 'ON' message
- or al,al ; test value
- jnz onof1 ; on, have right msg
- mov si,offset offmsg
- mov cx,3
- onof1: rep movsb ; copy right message in
- ret
- onoff endp
-
- ; print first message if false, second if true
- msg2 proc near
- call stval ; get value cell
- mov al,[si]
- mov si,[bx].msg ; assume off
- or al,al ; is it?
- jz msg21 ; yes, continue
- mov si,[bx].val2 ; else use alternate message
- msg21: jmp stms1 ; handle copy and return
- msg2 endp
-
- ; search a keyword table for a value, print that value
- srchkw proc near
- call stmsg ; first print message
- call stval
- mov al,[si] ; get value to hunt for
- mov ah,0 ; high order is 0
- mov bx,[bx].val2 ; this is table address
- jmp prttab ; and look in table
- srchkw endp
-
- ; search a keyword table for a bit value, print that value. [jrd]
- srchkb proc near
- call stmsg ; first print message
- call stbval ; get bit set or reset
- mov ah,0 ; al has 0/1, high order is 0
- mov bx,[bx].val2 ; this is table address
- jmp prttab ; and look in table
- srchkb endp
-
- ; get address of test value in stent. Returns address in si. [jrd]
- stbval proc near
- mov si,[bx].basval ; get address of test value
- cmp si,0 ; any there?
- je stbva1 ; no, quit with no match
- mov ax,[si] ; get value
- test ax,[bx].tstcel ; bit test value against data word
- jz stbva1 ; z = they don't match
- mov ax,1 ; match
- ret
- stbva1: mov ax,0 ; no match
- ret ; and return it
- stbval endp
-
-
- ; Print the drive name
- drnum proc near
- call stmsg ; copy message part first
- call stval ; pick up test value address
- mov ah,gcurdsk ; Get current disk
- int dos
- inc al ; We want 1 == A (not zero)
- mov curdsk,al
- add al,'@' ; Make it printable
- cld
- stosb
- mov word ptr [di],'\:'
- add di,2 ; end with a colon and backslash
- mov byte ptr [di],0 ; terminate in case drive is not ready
- mov dl,0 ; get current drive
- mov ah,gcd ; get current directory
- mov si,di ; current working buffer position
- int dos
- push cx
- push dx
- mov dx,di ; directory string
- call strlen ; length of path part to cx
- cmp cx,26 ; too long to show the whole thing?
- jbe drnum3 ; be = is ok, show the whole path
- push di ; scan backward for last backslash
- mov al,'\' ; thing to search for
- std ; backward
- mov di,si ; start of buffer
- add di,cx ; length of string
- repne scasb ; scan backward for a backslash
- jcxz drnum2 ; should not happen, but then again
- repne scasb ; do again for second to last path part
- drnum2: cld ; reset direction flag
- dec di ; move di two places preceding backslash
- mov [di],'--' ; insert a missing path indicator
- dec di
- mov byte ptr [di],'-'
- mov si,di ; we will show just this part
- pop di ; recover main status pointer
- drnum3: pop dx
- pop cx
-
- drnum4: lodsb ; copy until null terminator
- stosb
- cmp al,0 ; end of string?
- jne drnum4 ; ne = no
- dec di ; offset inc of stosb
- ret
- drnum endp
-
-
- ; Print the screen-dump filename [jrd]
-
- pasz proc near
- call stmsg ; copy message part
- mov si,[bx].val2 ; address of asciiz string
- pasz1: lodsb ; get a byte
- cmp al,0 ; at end yet?
- je pasz2 ; e = yes
- stosb ; store in buffer
- jmp short pasz1 ; keep storing non-null chars
- pasz2: ret
- pasz endp
-
- ; print the End-of-Line characters
- preol proc near
- call stmsg ; display leadin part of message
- mov al,dtrans.seol ; send eol char
- add al,40H ; make it printable
- stosb
- mov si,offset mseol2 ; second part of message
- call stms1 ; add that
- mov al,trans.reol ; receive eol char
- add al,40H ; make it printable
- stosb
- ret
- preol endp
-
- ; print Send Delay and Pause
- prsnd proc near
- call stmsg ; display leadin part of msg
- mov al,trans.sdelay ; Send Delay (sec)
- xor ah,ah
- call outnum
- ; mov si,offset sndmsg2 ; second part of msg
- mcmsgsi sndmsg2,csndmsg2
- call stms1 ; add that
- mov al,spause ; Send Pause (millisec)
- call outnum
- ; mov si,offset sndmsg3 ; last part of msg
- mcmsgsi sndmsg3,csndmsg3
- call stms1 ; add it too
- ret
- prsnd endp
-
- ; Print the handshake
- prhnd:
- ; mov si,offset handst ; copy in initial message
- mcmsgsi handst,chandst
- call stms1
- ; mov si,offset nonmsg ; assume no handshake
- mcmsgsi nonmsg,cnonmsg
- mov bx,portval
- cmp [bx].hndflg,0 ; Is handshaking in effect?
- jne prh0 ; Yes, print what we're using
- jmp stms1 ; no, say so and return
- prh0: mov al,5eh ; Doing handshaking with control char
- stosb
- mov al,[bx].hands
- add al,40H ; Make printable
- stosb ; put in buffer
- ret ; and return
-
- ; Print the pad character in AL
- prpad: cmp al,127 ; Are they using a delete?
- jne prpad0
- mov ah,prstr
- ; mov dx,offset delmsg
- mcmsg delmsg,cdelmsg
- int dos
- ret
- prpad0: mov dl,5eh ; caret
- mov ah,conout
- push ax
- int dos
- pop ax
- mov dl,al
- add dl,40H ; Make printable
- int dos
- ret
-
- ; Print value from table. BX/address of table, AL/value of variable
- prttab: push cx ; save column count
- mov cl,[bx] ; Number of entries in our table
- inc bx ; Point to the data
- prtt0: mov dl,[bx] ; Length of keyword
- inc bx ; Point to keyword
- mov dh,0
- inc dx ; Account for "$" in table
- mov si,dx ; Put to index register
- cmp ax,[bx+si] ; Is this the one?
- je prtt1
- add bx,dx ; Go to end of keyword
- add bx,2 ; Point to next keyword
- dec cl ; Any more keywords to check?
- jnz prtt0 ; Yes, go to it
- ; mov bx,offset prterr
- mcmsgb prterr,cprterr
- prtt1: mov si,bx
- pop cx ; recover column count
- jmp stms1 ; copy in message
-
- ; Print the baud rate
-
- BAUDPRT PROC NEAR
- ; mov si,offset baudrt ; "Baud rate is"
- mcmsgsi baudrt,cbaudrt
- call stms1 ; display that part
- call getbaud ; read baud rate first
- mov bx,portval
- mov ax,[bx].baud
- cmp al,byte ptr bdtab ; number of table entries
- jb bdprt5 ; b = in table
- ; mov si,offset unrec ; say unrecognized value
- mcmsgsi unrec,cunrec
- jmp stms1 ; display text and return
- bdprt5: mov bx,offset bdtab ; show ascii rate from table
- call prttab
- ret
- BAUDPRT ENDP
-
- ; display Take/Macro COUNT
- stcnt proc near
- call stmsg ; display leadin part of msg
- cmp taklev,0 ; in a Take file or macro?
- jne stcnt1 ; ne = yes
- ; mov si,offset nonemsg ; say none
- mcmsgsi nonemsg,cnonemsg
- call stms1
- ret
- stcnt1: push bx
- mov bx,takadr ; current Take structure
- mov ax,[bx].takctr ; get COUNT
- pop bx
- call outnum
- ret
- stcnt endp
-
- ; ALARM time
- stalr proc near
- call stmsg ; display leading part of msg
- push bx ; preserve register
- mov bx,0 ; position index
- stalr1: push bx ; save around calls
- cmp alrhms[bx],10 ; two digits?
- jae stalr2 ; ae = yes
- mov al,'0'
- stosb ; show leading zero
- stalr2: mov al,alrhms[bx] ; show time component
- mov ah,0
- call outnum
- pop bx ; recover index
- inc bx
- cmp bx,3 ; done all fields?
- jae stalr3 ; ae = yes
- mov al,':'
- stosb
- jmp short stalr1 ; do next field
- stalr3: pop bx
- ret
- stalr endp
-
- ; Jumping to this location is like retskp. It assumes the instruction
- ; after the call is a jmp addr
-
- RSKP PROC NEAR
- pop bp
- add bp,3
- push bp
- ret
- RSKP ENDP
-
- ; Jumping here is the same as a ret
-
- R PROC NEAR
- ret
- R ENDP
-
- ; routine to print an error message, then retskp
- ; expects message in dx
- reterr proc near
- mov ah,prstr
- int dos
- jmp rskp
- reterr endp
-
- code ends
- ;CHINESE2
- ifdef MSDOS
- include mssset2.dat
- else
- include ccsset2.dat
- endif
-
- if1
- %out [End of pass 1]
- else
- %out [End of assembly]
- endif
- end
-